home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
2.2
/
Dhrystones.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
14KB
|
525 lines
" NAME Dhrystones
AUTHOR TPH@cs.man.ac.uk
FUNCTION rough comparison benchmark for ST vs other langs
ST-VERSIONS 2.2
PREREQUISITES
CONFLICTS
DISTRIBUTION world
VERSION 1.1
DATE 22 Jan 1989
SUMMARY Dhrystones
is a transliteration from the Dhrystone benchmarks in 'C' (ugh!)
to Smalltalk. This code is not particularly representative of typical
Smalltalk programs, but may provide a non-rigorous comparison between
Smalltalk-80 and other programming languages/environments.(2.2).TPH
"!
'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:02:18 pm'!
Object subclass: #ObjectF1
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!ObjectF1 methodsFor: 'actions'!
with: charPar1 and: charPar2
"Performs some charactor comparisons, and returns
an integer (was an enum)."
| charLoc1 charLoc2 |
charLoc1 _ charPar1.
charLoc2 _ charPar2.
(charLoc1 ~= charLoc2) ifTrue: [^1] ifFalse: [^2]! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:02:21 pm'!
Object subclass: #ObjectF2
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!ObjectF2 methodsFor: 'actions'!
strcmp: str1 with: str2
"A C strcmp look-alike. Answers with the
difference between the characters at the first
position where the strings are different."
| i l1 l2 |
i _ 1.
l1 _ str1 size.
l2 _ str2 size.
[(str1 at: i) = (str2 at: i)] whileTrue: [
i _ i + 1.
(i > l1)
ifTrue: [(i > l2) ifTrue: [^0] ifFalse: [^(0 - (str2 at: i) asInteger)]]
ifFalse: [(i > l2) ifTrue: [^((str1 at: i) asInteger)]]
].
^((str1 at: i) asInteger - (str2 at: i) asInteger)!
with: strParI1 and: strParI2
"Performs some string type operations, and returns a boolean result."
| intLoc charLoc f1 |
f1 _ ObjectF1 new.
intLoc _ 1.
[intLoc <= 1] whileTrue: [
((f1 with: (strParI1 at: intLoc) and: (strParI2 at: (intLoc + 1))) = 1) ifTrue: [
charLoc _ $A.
intLoc _ intLoc + 1].
((charLoc >= $W) & (charLoc <= $Z)) ifTrue: [intLoc _ 7].
(charLoc = $X)
ifTrue: [^true]
ifFalse: [
((self strcmp: strParI1 with: strParI2) > 0)
ifTrue: [intLoc _ intLoc + 7. ^true]
ifFalse: [^false]
]
]! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:02:26 pm'!
Object subclass: #ObjectF3
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!ObjectF3 methodsFor: 'actions'!
with: enumParIn
"Part of the Dhrystone benchmarks. Performs a
simple test on integers and returns a boolean.
C version used enums."
| enumLoc |
enumLoc _ enumParIn.
(enumLoc = 3) ifTrue: [^true].
^false
"This would be better written as:
^(enumLoc = 3)
but the above is a direct translation from the C program."! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:01:26 pm'!
Link subclass: #DhryRecord
instanceVariableNames: 'discr enumComp intComp stringComp '
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!DhryRecord methodsFor: 'variable access'!
discr
^discr!
discr: anInteger
discr _ anInteger!
enumComp
^enumComp!
enumComp: anInteger
enumComp _ anInteger!
intComp
^intComp!
intComp: anInteger
intComp _ anInteger!
stringComp
^stringComp!
stringComp: aString
stringComp _ aString! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:02:07 pm'!
Object subclass: #Object6
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object6 methodsFor: 'actions'!
with: enumParIn
"Part of the Dhrystone benchmarks. Uses integers instead
of C enums. Equivalent of a switch statement. Returns
an integer."
| enumParOut |
enumParOut _ enumParIn.
(ObjectF3 new with: enumParIn) ifFalse: [enumParOut _ 4].
(enumParIn = 1) ifTrue: [^enumParOut _ 1].
(enumParIn = 2) ifTrue: [
(Dhrystone intGlob > 100) ifTrue: [^enumParOut _ 1]
ifFalse: [^enumParOut _ 4]].
(enumParIn = 3) ifTrue: [^enumParOut _ 2].
(enumParIn = 4) ifTrue: [^enumParOut].
(enumParIn = 5) ifTrue: [^enumParOut _ 3].! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:01:55 pm'!
Object subclass: #Object3
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object3 methodsFor: 'actions'!
doit
"Part of the Dhrystone benchmarks. Performs
some operations on LinkedLists and returns a Link."
| parOut |
Dhrystone record notNil
ifTrue: [parOut _ Dhrystone record first]
ifFalse: [Dhrystone intGlob: 100].
parOut intComp: (Object7 new with: 10 and: (parOut intComp)).
^parOut! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:01:45 pm'!
Object subclass: #Object1
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object1 methodsFor: 'actions'!
with: recordIn
"Part of the dhrystone benchmarks. Uses a LinkedList, rather
than the 'C' structures and pointers."
"This bit is in many ways the least satisfactory part of the
translation from 'C' to Smalltalk. Suggestions on how it might
be improved are welcomed."
recordIn first intComp: 5.
recordIn first nextLink intComp: (recordIn first intComp).
Object3 new doit.
(recordIn first nextLink discr = 1)
ifTrue:
[recordIn first nextLink intComp: 6.
recordIn first nextLink enumComp:
(Object6 new with: (recordIn first nextLink enumComp)).
recordIn first nextLink intComp:
(Object7 new with: 10 and: (recordIn first nextLink intComp))]! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:01:50 pm'!
Object subclass: #Object2
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object2 methodsFor: 'actions'!
with: intParIO
"Part of the Dhrystone benchmarks. Performs some
operations on integers and characters, and returns an integer."
| intLoc enumLoc temp | "temp not necessary in C version."
intLoc _ intParIO + 10.
[true] whileTrue: [
(Dhrystone char1Glob = $A) ifTrue: [
intLoc _ intLoc - 1.
temp _ intLoc - Dhrystone intGlob.
enumLoc _ 1].
(enumLoc = 1) ifTrue: [^temp]
].! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:01:58 pm'!
Object subclass: #Object4
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object4 methodsFor: 'actions'!
doit
"Performs part of the Dhrystone benchmark code."
| boolLoc |
boolLoc _ ((Dhrystone char1Glob) = $A).
boolLoc _ boolLoc | (Dhrystone char1Glob).
Dhrystone char2Glob: $B! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:02:04 pm'!
Object subclass: #Object5
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object5 methodsFor: 'actions'!
doit
"Performs part of the Dhrystone benchmark code."
Dhrystone char1Glob: $A.
Dhrystone boolGlob: false! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:02:11 pm'!
Object subclass: #Object7
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object7 methodsFor: 'actions'!
with: intParI1 and: intParI2
"Part of the Dhrystone benchmarks. Performs some
arithmetic, and answers with an integer."
| intLoc |
intLoc _ intParI1 + 2.
^intParI2 + intLoc! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:02:13 pm'!
Object subclass: #Object8
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
!Object8 methodsFor: 'actions'!
with: array1Par with: array2Par with: intParI1 with: intParI2
"Part of the Dhrystone benchmarks. Performs some operations
on arrays."
| intLoc intIndex |
intLoc _ intParI1 + 5.
array1Par at: intLoc put: intParI2.
array1Par at: (intLoc + 1) put: (array1Par at: intLoc).
array1Par at: (intLoc + 30) put: intLoc.
intIndex _ intLoc.
[intIndex <= (intLoc + 1)] whileTrue: [
(array2Par at: intLoc) at: intIndex put: intLoc.
intIndex _ intIndex + 1].
(array2Par at: intLoc) at: (intLoc - 1) put:
(((array2Par at: intLoc) at: (intLoc - 1)) + 1).
(array2Par at: (intLoc + 20)) at: intLoc put: (array1Par at: intLoc).
Dhrystone intGlob: 5.! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:01:38 pm'!
Object subclass: #Object0
instanceVariableNames: 'intLoc1 intLoc2 intLoc3 charLoc charIndex enumLoc string1Loc string2Loc '
classVariableNames: ''
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
Object0 comment:
'This contains the outer loop of the Dhrystone benchmark
code.'!
!Object0 methodsFor: 'actions'!
doit
"Repeatedly perform the code inside the benchmark loop.
Answer with the time (in milliseconds) taken for all the loops."
| time |
time _ Time millisecondsToRun: [
Dhrystone loopCount timesRepeat: [
Object5 new doit.
Object4 new doit.
intLoc1 _ 2.
intLoc2 _ 3.
string2Loc _ 'DHRYSTONE PROGRAM, 2''ND STRING'.
enumLoc _ 2.
Dhrystone boolGlob: (ObjectF2 new with: string1Loc and: string2Loc) not.
[intLoc1 < intLoc2] whileTrue: [
intLoc3 _ 5 * intLoc1 - intLoc2.
intLoc3 _ Object7 new with: intLoc1 and: intLoc2.
intLoc1 _ intLoc1 + 1].
Object8 new
with: Dhrystone array1Glob
with: Dhrystone array2Glob
with: intLoc1 with: intLoc3.
Object1 new with: Dhrystone record.
charIndex _ $A.
[charIndex <= Dhrystone char2Glob] whileTrue: [
charIndex _ (charIndex asInteger + 1) asCharacter.
(enumLoc = (ObjectF1 new with: charIndex and: $C)) ifTrue: [
enumLoc _ Object6 new with: 1]].
intLoc3 _ intLoc2 * intLoc1.
intLoc2 _ intLoc3 / intLoc1.
intLoc2 _ 7 * (intLoc3 - intLoc2) - intLoc1.
intLoc1 _ Object2 new with: intLoc1
]
].
^time asFloat! !
!Object0 methodsFor: 'private'!
initialize
"Sets up some of the instance variables (once only),
corresponding to locals in the 'C' version, and some class
variables, corresponding to globals in the 'C' version."
"Pointers to next record and similar things actually
done by a LinkedList and Links, which are created
in Dhrystone class initialize."
Dhrystone record first discr: 1.
Dhrystone record first enumComp: 3.
Dhrystone record first intComp: 40.
Dhrystone record first stringComp: 'DHRYSTONE PROGRAM, SOME STRING'.
string1Loc _ 'DHRYSTONE PROGRAM, 1''ST STRING'.
(Dhrystone array2Glob at: 8) at: 7 put: 10! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Object0 class
instanceVariableNames: ''!
!Object0 class methodsFor: 'instance creation'!
new
^super new initialize! !'From Smalltalk-80, version 2, of April 1, 1983 on 9 April 1987 at 2:01:30 pm'!
Object subclass: #Dhrystone
instanceVariableNames: 'loopTime '
classVariableNames: 'Array1Glob Array2Glob BoolGlob Char1Glob Char2Glob IntGlob LoopCount Record '
poolDictionaries: ''
category: 'Dhrystone Benchmarks'!
Dhrystone comment:
'This class, and the related classes (Object0, Object1 and so
on), form a tranliteration of the Dhrystone (V1.1) benchmarks from ''C''
into Smalltalk--80. Accesses to ''C'' local variables have been
replaced by accesses of instance variables, or by accesses to
temporary variables. Accesses to ''C'' globals have been replaced by
accesses to instance variables in other objects, using message sends.
''C'' function calls have been replaced by the creation of
some objects which then execute some code.
The code is as direct a transliteration as possible; it is
not particularly typical of Smalltalk code.
While this benchmark is not tailored to Smalltalk in any way,
it does provide a (non-rigorous) point of comparison
between Smalltalk-80 implementations. It may also be useful when
comparing Smalltalk with other systems.
'!
!Dhrystone methodsFor: 'private'!
calculateNullLoopTime
"Calculate the time taken by a loop which does nothing."
loopTime _ (Time millisecondsToRun: [
Dhrystone loopCount timesRepeat: []]) asFloat.! !
!Dhrystone methodsFor: 'actions'!
doit
"Perform the Dhrystone loops. Print the result in
the System Transcript."
| runTime benchTime |
Transcript cr; cr; show: 'Running Dhrystone benchmark (Smalltalk version)....'.
runTime _ Object0 new doit.
benchTime _ ((runTime - loopTime) / 1000).
Transcript cr; show: 'Time for ', Dhrystone loopCount printString.
Transcript show: ' passes = ',(benchTime printString),' seconds.'.
Transcript cr; show: 'This system benchmarks at '.
Transcript show: (Dhrystone loopCount / benchTime) printString.
Transcript show: ' dhrystones/second.'.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Dhrystone class
instanceVariableNames: ''!
!Dhrystone class methodsFor: 'class access'!
array1Glob
^Array1Glob!
array1Glob: anArray
Array1Glob _ anArray!
array2Glob
^Array2Glob!
array2Glob: anArray
Array2Glob _ anArray!
boolGlob
^BoolGlob!
boolGlob: aBoolean
BoolGlob _ aBoolean!
char1Glob
^Char1Glob!
char1Glob: aChar
Char1Glob _ aChar!
char2Glob
^Char2Glob!
char2Glob: aChar
Char2Glob _ aChar!
intGlob
^IntGlob!
intGlob: anInteger
IntGlob _ anInteger!
loopCount
"Answers with the number of times the loop is
to be repeated."
^LoopCount!
record
"Answers with the LinkedList used instead of the structures
in the original C code."
^Record! !
!Dhrystone class methodsFor: 'class initialization'!
initialize
"Initialize the class variables, corresponding to globals
in the 'C' version."
LoopCount _ 50000. "Number of iterations used."
"Set this value to 500000
for much better accuracy,
but only if you can wait all day!!"
IntGlob _ 0.
Array1Glob _ Array new: 50.
Array2Glob _ Array new: 50.
1 to: Array2Glob size do: [:each | Array2Glob at: each put: (Array new: 50)].
(Array2Glob at: 8) at: 7 put: 10.
Record _ LinkedList new.
Record addLast: DhryRecord new.
Record addLast: DhryRecord new.
"Dhrystone initialize."! !
!Dhrystone class methodsFor: 'instance creation'!
new
"Creates a new instance of the Dhrystone benchmark."
^super new calculateNullLoopTime
"Dhrystone initialize."
"Dhrystone new doit."! !
Dhrystone initialize!